COMP3141 Software System Design and Implementation

COMP3141: Software System Design and Implementation

Term 2, 2023

Code and Notes (Week 8 Wednesday)

Table of Contents

1 Live code

This is all the code I wrote during the lecture. No guarantee that it makes any sense out of context.

1.1 Haskell code

module W8a where

hello :: IO()
hello = putStrLn "Hello world!"

{- That doesn't seem so bad?
   Why not do that earlier?

   Because IO is a monad.

   Therefore:
    the way that you compose
    IO computations into more complex
    computations
    is by using monad bind!
 -}

chatty :: IO()
chatty = do
  putStrLn "Hello!!"
  putStrLn "What's your favourite dinosaur?"
  xs <- getLine
  putStrLn ("Oh " ++ xs ++ "!!")
  putStrLn "That's so cool that's mine too!"

chatty' :: IO()
chatty' =
  putStrLn "Hello!!" >>= \_ ->
  putStrLn "What's your favourite dinosaur?" >>= \_ ->
  getLine >>= \xs ->
  putStrLn ("Oh " ++ xs ++ "!!")  >>= \_ ->
  putStrLn "That's so cool that's mine too!"

{- In most languages,
   writing out an effectful statement,
   is the same thing as executing that statement.

   IO in Haskell is different:
    IO-computations are values that we can use same as
    any other value:
    - return them from functions
    - give them as arguments to functions
    - put them in lists...
   ^ Manipulating IO compuations as values in this way
     is *not* the same thing as executing them.
 -}

funky_program :: IO Int
funky_program =
  let todo_list :: [IO ()]
      todo_list = [putStrLn "Hello world",
                   putStrLn "Hello again world"]
  in do
    putStrLn "Oh no I have a huge todo list!!"
    head todo_list
    return $ length todo_list

less_funky_program :: IO Int
less_funky_program =
  let todo_list :: [IO ()]
      todo_list = [putStrLn "Hello world",
                   putStrLn "Hello again world"]
  in
    putStrLn "Oh no I have a huge todo list!!" >>= \_ ->
    sequence_ todo_list >>= \_ ->
    return $ length todo_list

{- We never write programs that actually perform IO
   Manipulating value with IO types is not the same
    thing as running the computation.

   Instead, the compiler (or interpreter) will run
   the IO computation that is in the main function.
 -}

{- Often, we have a list (or other form of sequence)
   of monad actions,
   and we want to run all of them

     mapM   :: Monad m => (a -> m b) -> [a] -> m [b]
     mapM_ :: Monad m => (a -> m b) -> [a] -> m ()

     -- execute a list of monad operations in sequence,
     -- accumulating the return values in a list
     sequence ::  Monad m => [m a] -> m [a]
     -- execute a list of monad operations in sequence,
     sequence_ :: Monad m => [m a] -> m ()
 -}

{- When you got the 2 at then,
    that was the repl displaying the return value,
    *not* my program producing side-effects
 -}


{- Suppose for the sake of argument that we had
 -}
unIO :: IO a -> a
unIO = undefined

{- This is a (fake) function that performs IO,
   but does not have IO anywhere in its type

   ^If you allow this sort of thing,
    - equational reasoning no longer works

         doStuff - doStuff = 0
         ^^^ this equation would be false in general
    - type signatures become less informative

    - if I see a Haskell type signature

         foo :: a -> a

      I *know* that this function (if it's total)
      can only be the identity function.

      But, if I had unIO,
        foo could perform arbitrary side effects.

    These facts are tremendously helpful in making
    Haskell programs tractable to reason about:
    - equational reasoning *always* works
    - type signatures tell us *a lot* about what
      the function is likely to do
    - the behaviour of foo can depend
      *only* on the function argument (and nothing else)
 -}
doStuff :: Int
doStuff =
  unIO $ do
    x <- getLine
    return $ read x

{- Q: so if IO can have side-effects,
      then isn't it the case that
      we can do equational reasoning *outside*
      the I/O monad, but it breaks *in* the I/O monad?
   A: No. Equational reasoning is always valid,
      including in the IO monad.
 -}


{- When I've been saying that in Haskell,
    equational reasoning always works.

   A more jargonny way to say that is:

    Haskell is referentially transparent.

   Referential transparency means:

    - If I have a program,
      I can replace any expression in the
      program with
        another expression that has
        the same value
      Without changing the meaning of the program.
 -}

getInt :: IO Int
getInt =
  do
    xs <- getLine
    return $ read xs

{- This version does not type check!
   getInt does *not* have type Int

   a computation that would return an int if executed,
   is (in Haskell) *not* the same thing as an Int
 -}
--version1 = getInt - getInt

version1 :: IO Int
version1 = do
  x <- getInt
  y <- getInt
  return $ x - y

version2 :: Int
version2 = 0

version3 :: IO Int
version3 = do
  x <- getInt
  return $ x - x
{- version1 and version3 are of comparable type,
   *but* they are not equal.
     version1 is a computation that reads from stdIn twice
     version2 is a computation that reads from stdIn once
 -}

{- version3         == (by definition)
   do x <- getInt
      return $ x -x
                    == (x-x = 0)
   do x <- getInt
      return $ 0    == (desugaring do notation)
   getInt >>= \x -> return $ 0 == (by definition of getInt)
   (getLine >>= \xs -> return $ read xs)
    >>= \x -> return $ 0 == (eta-associativity)
   getLine >>= (\xs -> (return $ read xs) >>= \x -> return $ 0)  == (left identity of >>=)
   getLine >>= (\xs -> return $ 0)

   version4

   the point: I *can* use equational reasoning to reason about I/O program
   here, I proved that the program is still the same if I inline the definition
   of getInt into the program.
   But this does *not* let me eliminate effectful steps.


   left identity:  return x >>= \x -> k x   ==   k x
   eta-associativity:   (m >>= \x -> k x) >>= \y -> k' y
                        == m >>= \x -> (k x >>= \y -> k' y)

   ^ as we do this equational reasoning,
     there is no rewrite rule we can apply
     to eliminate the I/O operation before the bind
 -}

{- Q:

    So is the idea behind why we can maintain referential
    transparency with IO that by using bind,
    x and y is no longer the "same thing",
    since they aren't "equal" to getInt?

   A: Yes.
 -}

applyTwice :: (a -> a) -> a -> a
applyTwice f = f . f

applyIOTwice :: IO a -> IO a
applyIOTwice io = io >>= \_ -> io

aBunchOfEithers :: [Either String Int]
aBunchOfEithers =
  [Left "a string",
   Right (-42),
   Left ""
   -- Right "a sstring"
  ]

{- You can use the Either monad to encode
   -- computations that may fail
      but yield error messages
   -- computations that may yield exceptions
 -}

data Exp = Int Int | Var String | Add Exp Exp | Div Exp Exp
  deriving (Eq,Show)

calculator :: [(String,Int)] -> Exp -> Either String Int
calculator env (Int n) = return n
calculator env (Var s) =
  case lookup s env of
    Just n  -> return n
    Nothing -> Left ("Undefined variable: " ++ s)
calculator env (Add e1 e2) =
  do
    n <- calculator env e1
    m <- calculator env e2
    return $ n + m
calculator env (Div e1 e2) =
  do
    n <- calculator env e1
    m <- calculator env e2
    if m == 0 then
      Left "Division by zero"
    else
      return $ n `div` m
{- Question: why didn't you write return(Right n)
   Answer: because return = Right   in the either monad

     return :: b -> Either a b
     return b = Right b

     (>>=) :: Either a b -> (b -> Either a c) -> Either a c
     Left x >>= _ = Left x
     Right x >>= k = k x

    *
   ***
  *****
 -}

generateTriangle :: Int -> [String]
generateTriangle n =
  do
    m <- [n,n-2..0]
    return $ replicate ((n-m) `div` 2) ' ' ++ replicate m '*'

triangle :: IO ()
triangle = do
  putStrLn "Give me a base width:"
  n <- getInt
  if n < 1 then do
    putStrLn "Number is too small!"
    triangle
  else do
    let lines = generateTriangle n
    mapM_ putStrLn (reverse lines)

1.2 Java code

import java.io.Console;

public class Hello {
    static Console console = System.console();

    static int getInt() {
        return Integer.parseInt(console.readLine());
    }

    static int selfSubtract(int x) {
        return x - x;
    }

    public static void main(String[] args) {
        System.out.println("Let's check if Java has referential transparency!");

        System.out.println("== VERSION 1 ==");

        System.out.println("The difference is " + (getInt() - getInt()));

        System.out.println("== VERSION 1.5 ==");

        System.out.println("The difference is " + selfSubtract(getInt());

        // If Java satisfied referential transparency
        // this next program would be equivalent:

        System.out.println("== VERSION 2 ==");
        System.out.println("The difference is " + 0);

        System.out.println("== VERSION 3 ==");
        int x = getInt();
        System.out.println("The difference is " + selfSubtract x);

        System.out.println("== VERSION 4 ==");
        int y = getInt();
        System.out.println("The difference is " + 0);

    }
}

2023-08-13 Sun 12:52

Announcements RSS